home
***
CD-ROM
|
disk
|
FTP
|
other
***
search
/
Shareware Grab Bag
/
Shareware Grab Bag.iso
/
015
/
scrnprt2.arc
/
LIB1.ASM
next >
Wrap
Assembly Source File
|
1985-06-22
|
17KB
|
632 lines
; -Macro Library Number 1
;******************* LIB1.ASM : Last Update: 2-8-85 **********
;
; MACROS AVAILABLE:
;------------------------------------------------------------------
; BINARY_TO_DISPLAY MACRO SOURCE, DEST
;Convert 16-bit binary SOURCE to ASCII string: DEST.
; CCALL MACRO COND,PROCNAME
;Conditional call macro
; CLS MACRO
;Scroll screen down
; DISPLAY MACRO TEXT
;Display from offset TEXT until '$' terminator.
; DISP_AT MACRO ROW,COLUMN,TEXT
;Locate cursor and display from offset TEXT
;until '$' terminator.
; DISPCHAR MACRO CHAR
;Display a single ASCII character, advance cursor.
; FILE_ERRMSG
;list of error messages for file I/O
; FILL_SCREEN MACRO CHAR,ATTRIBUTE,COUNT
;Fill memory-mapped screen with char, attribute.
;COUNT defaults to 2078, entire screen.
; INKEY MACRO
;Input a single keystroke, returned in AH:AL
; INPUT BUFFER,COUNT
; Input a string from the keyboard, terminated by a 0.
; KYBD_BINB MACRO DEST_BYTE
;Accepts input byte (0-255) from keyboard, and converts
;to binary in DEST_BYTE
; LOCATE MACRO ROW,COLUMN
;Locate cursor at ROW, COLUMN
; SCROLL_WINDOW MACRO ULR,ULC,LRR,LRC,ATTRIB
; SCROLLDN MACRO ULR,ULC,LRR,LRC
;Scroll screen down 1 line
; SCROLLUP MACRO ULR,ULC,LRR,LRC
;Scroll screen up 1 line
; SETDATA MACRO DATASEG
;For .EXE files only: Start of Data Segment passed
; SHAPE MACRO TABLE, ROW, COLUMN
; This Macro prints a shape on the screen made up of ASCII
; graphics characters. TABLE is the offset of the shape table.
; If ROW, COL omitted, the shape starts at 12,40.
; Shape Table format:
; 1 Character to plot
; 1 Attribute
; 1 Row offset from last character
; 1 Column offset from last character
; WINDOW MACRO ULR,ULC,LRR,LRC
;Print window on screen, giving corner coordinates
; WRITESTR macro
;This displays a string terminated by 00H
; //////////////////////////////////////////////////////////////////
; \\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\
;------------------------ FILE_ERRMSG -----------------------
; This is a list of error messages in the FILE_IO library
;
;
file_errmsg macro
; (address table of messages)
emess dw m1,m2,m3,m4,m5,m6,m7,m8,m9,m10,m11,m12,m13,m14
dw m15,m16,m17,m18
m1 db cr,lf,'Invalid function number',cr,lf,0
m2 db cr,lf,'File not found',cr,lf,0
m3 db cr,lf,'Path not found',cr,lf,0
m4 db cr,lf,'Too many open files',cr,lf,0
m5 db cr,lf,'Access denied',cr,lf,0
m6 db cr,lf,'Invalid handle',cr,lf,0
m7 db cr,lf,'Memory control blocks destroyed',cr,lf,0
m8 db cr,lf,'Insufficient memory',cr,lf,0
m9 db cr,lf,'Invalid memory block address',cr,lf,0
m10 db cr,lf,'Invalid environment',cr,lf,0
m11 db cr,lf,'Invalid format',cr,lf,0
m12 db cr,lf,'Invalid access code',cr,lf,0
m13 db cr,lf,'Invalid data',cr,lf,0
m14 db cr,lf,'Message not in use',cr,lf,0
m15 db cr,lf,'Invalid drive was specified',cr,lf,0
m16 db cr,lf,'Attempted to remove the current directory',cr,lf,0
m17 db cr,lf,'Not same device',cr,lf,0
m18 db cr,lf,'No more files',cr,lf,0
endm ;----- end of macro ------
;-------------------------------------------------------
; INPUT (buffer, length)
; This macro accepts input from the keyboard, storing
; the result at Buffer+2. The length count causes a
; row of periods (.) to display the length of the field.
input macro buffer,length
local dot, display_input_field, crlf, start
jmp start
crlf DB 0dH,0aH,0
start: push ax
push bx
push cx
push dx
push di
display_input_field:
xor bh,bh ; video page zero
mov cx,length ; display a row of periods (.)
mov al,'.'
mov ah,0AH ; display multiple characters
int 10H ; bios INT 10H video function
mov al,0 ; fill buffer with zeros
lea di,buffer
mov cx,length + 1 ; one extra for CR at eol
repnz stosb
mov ah,0AH ; keyboard input
mov buffer,length+1 ; put max length at head
mov DX,offset buffer
int 21H
pop di ; restore all registers
pop dx
pop cx
pop bx
pop ax
writestr crlf ; print a carriage return
endm
;-----------------------------------------------------------
; This Macro prints a horizontal line, using the string
; pointed to by [DI] directly into the screen buffer.
; On entry: DS:BX = offset of screen buffer location.
;-----------------------------------------------------------
PRINT_LINE MACRO left,mid,right,len
local m1
push BX
push CX
xor CX,CX
mov CL,len ;use as a loop count
mov AL,left ;1st char.
mov [BX],AL ;store in memory
add BX,2 ;next screen location
mov AL,mid
m1: mov [BX],AL ;store in memory
add BX,2 ;next screen location
loop m1
mov AL,right ;last char.
mov [BX],AL
pop CX
pop BX
ENDM
;--------------------------------- WINDOW ---------------------
; Draw window on screen, giving upper-left and lower-right
; corners.
;--------------------------------------------------------------
WINDOW MACRO ULR,ULC,LRR,LRC
local top,mid,bot
push AX
push BX
push CX
push DS ;save current DS value
mov AX,0B000H
mov DS,AX
mov BX,(ULR-1)*160 ;BX points to screen buffer
add BX,(ULC-1)*2
wid = (LRC-ULC-1) ;"width" is a reserved word
height = (LRR-ULR-1)
top: print_line 0C9H,0CDH,0BBH,wid
xor CX,CX
mov CL,height
mid: add BX,160 ;next line in screen buffer
print_line 0BAH,20H,0BAH,wid
loop mid
bot: add BX,160
print_line 0CAH,0CDH,0BCH,wid
pop DS ;retrieve DS register
pop CX
pop BX
pop AX
ENDM
;----------------------- INKEY --------------------------------
; Get keystroke, place in AL.
; On exit: AH=1, AL=key for normal keys.
; For extended codes, AH=FF, AL=extended code.
;---------------------------------------------------------------
INKEY MACRO CHAR
local norm,ext,done
mov AH,7 ;read kybd, no echo
int 21H
or AL,AL ;extended code?
jz ext
norm: mov AH,1 ;signal normal ASCII char.
jmp done ;and exit
ext: int 21H ;read 2nd character of extended code
mov AH,0FFH ;signal extended code
done: nop
endm
;---------------- BINARY_TO_DISPLAY -----------------------
; On entry: Source = 16-bit signed binary value
; Dest = ASCII result string
;------------------------------------------------------------
BINARY_TO_DISPLAY MACRO SOURCE, DEST
local fill,clr_dvd,exit_binary_to_display
push AX
push BX
push CX
push DX
push SI
mov AX,SOURCE ;original Binary number
push AX ;preserve the number
mov BX,OFFSET DEST ;offset of ASCII string
mov CX,6 ;6 digits = max. length
fill: mov byte ptr [BX],' ' ;fill with blanks
inc BX
loop fill
mov SI,10 ;will divide by 10
or AX,AX
jns clr_dvd ;negative?
neg AX ;yes- make it positive
clr_dvd:
xor DX,DX
div SI ;divide AX by 10 (rem. in DX)
add DX,30H ;convert remainder to ASCII
dec BX ;reverse thru ascii_result
mov [BX],DL ;store ASCII character
inc CX ;count length of string
or AX,AX ;AX = 0?
jnz clr_dvd ;no - divide again
pop AX ;yes -retrieve original number
or AX,AX ;was it negative?
jns exit_binary_to_display
dec BX ;yes - store a "-" sign
mov byte ptr [BX],'-'
inc CX
exit_binary_to_display: ;(AX was popped)
pop SI
pop DX
pop CX
pop BX
pop AX
ENDM
; (SCROLL_WINDOW)
; Parameters: Upper Left Row, Upper left column, Lower right row,
; Lower right column, Num lines to clear, Attribute of blank lines
; Entire screen cleared if all parameters omitted.
Scroll_window MACRO ULR,ULC,LRR,LRC,LINES,ATTRIB
PUSH AX
PUSH BX
PUSH CX
PUSH DX
MOV AH,7 ;Scroll down function
MOV AL,LINES ;Num lines to scroll
IFB <LINES> ;If LINES omitted, scroll entire
MOV AL,0 ; window.
ENDIF
MOV CH,ULR ;Upper left row
MOV CL,ULC ;Upper left column
IFB <ULC> ;If upper left omitted, choose
MOV CX,0 ; 0,0 as upper left corner.
ENDIF
MOV DH,LRR ;Lower right row
MOV DL,LRC ;Lower right column
IFB <LRC> ;If lower right omitted, choose
MOV DX,184FH ; 24,79 as lower right corner.
ENDIF
MOV BH,ATTRIB ;Attribute of blank lines
IFB <ATTRIB> ;If attribute omitted, choose
MOV BH,7 ; normal attribute
ENDIF
INT 10H ;Call BIOS to do the job
POP DX ;Restore scratch registers
POP CX
POP BX
POP AX
ENDM
;-------------------------- CLS ----------------------------------
; Clears the entire screen
;
Cls MACRO
PUSH AX
PUSH BX
PUSH CX
PUSH DX
MOV AH,7 ; Scroll down function
MOV AL,0 ; 0 = entire window
MOV CX,0 ; 0,0 as upper left corner.
MOV DX,184FH ; 24,79 as lower right corner.
MOV BH,7 ; normal attribute
INT 10H ; Call BIOS
POP DX ; Restore scratch registers
POP CX
POP BX
POP AX
ENDM
;-------------------------- SCROLLUP ----------------------
; Scroll window up one line. All 4 parameters must be included.
SCROLLUP MACRO ULR,ULC,LRR,LRC
PUSH AX
PUSH BX
PUSH CX
PUSH DX
MOV AX,0601H ;Scroll up one line
MOV CH,ULR ;Upper left row
MOV CL,ULC ;Upper left column
MOV DH,LRR ;Lower right row
MOV DL,LRC ;Lower right column
MOV BH,7 ; normal attribute
INT 10H ;Call BIOS to do the job
POP DX ;Restore scratch registers
POP CX
POP BX
POP AX
ENDM
;-------------------------- SCROLLDN ----------------------
; Scroll window donw one line. All 4 parameters must be
; included.
SCROLLDN MACRO ULR,ULC,LRR,LRC
PUSH AX
PUSH BX
PUSH CX
PUSH DX
MOV AX,0701H ;Scroll down one line
MOV CH,ULR ;Upper left row
MOV CL,ULC ;Upper left column
MOV DH,LRR ;Lower right row
MOV DL,LRC ;Lower right column
MOV BH,7 ; normal attribute
INT 10H ;Call BIOS to do the job
POP DX ;Restore scratch registers
POP CX
POP BX
POP AX
ENDM
;--------------------------- LOCATE -----------------------
LOCATE MACRO ROW,COLUMN
PUSH AX
PUSH BX
PUSH DX
XOR BX,BX ;New: added 4-30-84, since the BX
; register must be cleared to 0 for
; the Interrupt to work correctly.
MOV AH,2 ;Function selected = locate
MOV DH,ROW
MOV DL,COLUMN
INT 10H ;Invoke BIOS to position cursor
POP DX
POP BX
POP AX
ENDM
;---------------------------- CCALL MACRO ------------------------
ccall macro cond,procname
Local L1,L2
J&cond L1
jmp L2
L1: call procname
L2: exitm
endm
;------------------------- DISPLAY -------------------------
DISPLAY MACRO TEXT ;'TEXT' is a passed parameter
PUSH AX
PUSH DX
MOV AH,9 ;Function selected-console output
MOV DX,OFFSET TEXT ;Point to message to print
INT 21H ;Request DOS service, ID in AH
POP DX
POP AX
ENDM
;----------------------- DISP_AT ---------------------------
; This Macro combines LOCATE and DISPLAY. If ROW and COLUMN
; are omitted, then 0,0 is assumed, but the leading commas
; must be supplied: DISP_AT ,,MSG1 (example)
DISP_AT MACRO ROW,COLUMN,TEXT
PUSH AX
PUSH BX
PUSH DX
XOR BX,BX
MOV AH,2 ;Function selected = locate
MOV DH,ROW
IFB <ROW>
MOV DH,0
ENDIF
MOV DL,COLUMN
IFB <COLUMN>
MOV DL,0
ENDIF
INT 10H ;Invoke BIOS to position cursor
MOV DX,OFFSET TEXT ;Offset from DS:
MOV AH,9 ;Select console output function
INT 21H ;Request DOS service
POP DX
POP BX
POP AX
ENDM
SETDATA MACRO DATASEG ;Start of Data Segment passed
PUSH DS ;Return addr of data seg on stack
MOV AX,0
PUSH AX ;Put zero offset return addr. on stack
MOV AX,DATASEG ;Initialize data segment
MOV DS,AX
ENDM
;
DISPCHAR MACRO CHAR
PUSH DX
PUSH AX
MOV DL,CHAR ;CHAR. TO BE PRINTED
MOV AH,02H ;REQUEST SINGLE CHAR. OUTPUT
INT 21H
POP AX
POP DX
ENDM
;----------------------- FILL_SCREEN --------------------------
; This Macro fills the screen with the ASCII code CHAR (0-255).
; ATTRIBUTE may be any of the following: normal (07H), normal w/
; high intensity (0FH), reverse (70H), reverse w/ high intensity
; (78H), normal+blink (87H), reverse+blink (F8H). See Scanlon
; text, p.251. If ATTRIBUTE omitted, normal is assumed. If
; COUNT omitted, then 2078 assumed.
FILL_SCREEN MACRO CHAR,ATTRIBUTE,COUNT
PUSH AX ;Save all scratch registers
PUSH CX
PUSH DX
PUSH DI
PUSH DS
MOV CX,COUNT ;Number of mem locations
IFB <COUNT> ;If COUNT is blank, set it
MOV CX,2078 ; to 2078 (full screen).
ENDIF
MOV DH,CHAR ;ASCII code to be output
MOV DL,ATTRIBUTE ;Attribute byte
IFB <ATTRIBUTE> ;If ATTRIBUTE is blank, set
MOV DL,0FH ; to 0F - normal display.
ENDIF
XOR DI,DI
MOV AX,0B000H ;Addr of text display card
MOV DS,AX ;Put screen addr in DS
STORE_CHAR:
MOV [DI],DH ;Store character
INC DI ;Point to attribute byte
MOV [DI],DL ;Store the attribute
INC DI
LOOP STORE_CHAR ;Continue until CX=0
POP DS
POP DI ;Restore all registers
POP DX
POP CX
POP AX
ENDM
;---------------------- KYBD_BINB -----------------------------
; This macro accepts any integer from the keyboard from 0-255,
; and stores it at DEST_BYTE in binary. If a larger number is
; desired, use the KYBD_BINW Macro (0-65535).
;--------------------------------------------------------------
KYBD_BINB MACRO DEST_BYTE
PUSH AX
PUSH BX
PUSH CX
MOV BX,0 ;BX will accumulate the digits
NEWCHAR:
MOV AH,1 ;DOS function for keyboard input
INT 21H
SUB AL,30H ;Convert the digit to Binary
JL EXIT_BINW ;Exit if value < 0
CMP AL,9 ;Is the digit > 9?
JG EXIT_BINW ;Yes. Must not be a decimal digit
CBW ;Convert byte in AL to word in AX
XCHG AX,BX ;Exch input digit & amount so far
MOV CX,10D
MUL CX ;Multiply amt collected by 10
XCHG AX,BX ;Store back in BX register
ADD BX,AX ;Add current digit to existing amt
JMP NEWCHAR ;Get another keyboard char.
EXIT_BINW:
MOV [DEST_BYTE],BL ;Store the result
POP CX ;Restore scratch registers
POP BX
POP AX
ENDM
;------------------------------------------------------
; WRITESTR macro
;
; This displays a string terminated by 00H
; String is an offset value.
;------------------------------------------------------
writestr macro string
local again,exit
push AX
push BX
push DX
mov AH,2 ;single char output
mov BX,offset string
again:
mov DL,[BX]
cmp DL,0 ;check for zero teminator
jz exit
int 21H
inc BX
jmp again
exit: pop DX
pop BX
pop AX
endm ;--------------------------------------------
;------------------------- SHAPE ----------------------------
SHAPE MACRO TABLE, ROW, COLUMN
; This Macro prints a shape on the screen made up of ASCII
; graphics characters. TABLE is the offset of the shape table,
; ROW and COLUMN are the optional starting location. If omitted,
; the shape starts at 12,40.
;---------------------------------------------------------------
SHAPE MACRO TABLE, ROW, COLUMN
MOV DI, OFFSET TABLE ;Point to start of table
MOV DH, ROW
MOV DL, COLUMN
IFB <COLUMN> ;If row & column omitted,
MOV DX, 0C28H ;Start at row 12, column 40
ENDIF
PUSH AX ;Save registers
PUSH BX
PUSH CX
PUSH DX
PUSH DI ;Save pointer to start of table
STI ;Enable interrrupts
MOV AH,15 ;Set BH to active display page
INT 10H
SUB CH,CH ;Clear high byte of count
MOV CL,[DI] ;CL holds character count
INC DI ;DI points to first character
NEXT_CHAR:
ADD DH,[DI+2] ;Update row pointer relative from
; last position
ADD DL,[DI+3] ;Also column pointer
MOV AH,2 ;Move cursor
INT 10H
MOV AL,[DI] ;Get ASCII code of character
MOV BL,[DI+1] ; and attribute.
PUSH CX ;Save character count
MOV CX,1 ;Write a single char. to screen
MOV AH,9 ;Function #9 for INT 10H
INT 10H
POP CX ;Restore character count
ADD DI,4 ;DI points to next character block
LOOP NEXT_CHAR ;Do another character until CX=0
POP DI ;Restore all registers
POP DX
POP CX
POP BX
POP AX
ENDM